home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Mac Mania 5
/
MacMania 5.toast
/
/
Tools&Utilities
/
Plotfoil 3.2
/
naca-1.0
/
naca4.f
< prev
next >
Wrap
Text File
|
1995-09-13
|
9KB
|
377 lines
c
c-----------------------------------------------------------------------------
c
c Naca4.f -- contains routines to generate the NACA four and five
c digit series foils, both in their original form, and
c with the modified thickness profiles.
c
c Written By: S.E.Norris
c
c norris@cfd.mech.unsw.edu.au
c
c $RCSfile: naca4.f,v $
c $Author: norris $
c $Revision: 1.3 $
c $Date: 1995/08/31 11:05:52 $
c
c $Log: naca4.f,v $
c Revision 1.3 1995/08/31 11:05:52 norris
c *** empty log message ***
c
c Revision 1.2 1995/08/31 06:11:57 norris
c Fixed divide error that was stuffing up on the Cray.
c
c Revision 1.1 1995/08/30 09:59:47 norris
c Initial revision
c
c-----------------------------------------------------------------------------
c
SUBROUTINE Naca4( x,npl,npmx,naca,inaca,scle,modified )
c
IMPLICIT none
INTEGER npl,npmx,inaca
REAL x(3,npmx),scle
CHARACTER naca*(*)
LOGICAL modified
c
c This routine calculates the ordinates of a NACA four digit foil.
c
INTEGER i,j
INTEGER npt,npf
REAL ndata(5),cf(3),ca(3),ct(5),dcf(2),dca(2)
REAL a(5),d(4)
REAL dx,dy,dydx,t,y
REAL Poly
EXTERNAL Poly
c
DATA ct / 0.0 ,-0.126 ,-0.3537 , 0.2843 ,-0.1015 /
c
c
npt = npl+1
npf = npl/2
c
c Set the x values according to a cosine distribution.
c
call cosdn( x,npl,npmx )
c
c Calculate the parameters describing the foil, from the given NACA
c number. Then calculate the polynomial coeffs for the camber.
c
call Naca4b( naca,inaca,ndata,modified )
call Naca4c( cf,dcf,ndata(1),ndata(2) )
call Naca4c( ca,dca,ndata(1),(1.0 - ndata(2)) )
if (modified) then
call Nacam( a,d,ndata(4) )
endif
c
c Calculate 'y' values for each value of 'x'.
c
x(2,1) = 0.0
x(2,npt) = 0.0
x(2,npf+1) = 0.0
do i = 2,npf
j = npt+1-i
c
c Calculate the camber line.
c
if (x(1,i).le.ndata(2)) then
y = Poly( x(1,i),2,cf )
dydx = Poly( x(1,i),1,dcf )
else
y = Poly(( 1.0 - x(1,i) ),2,ca )
dydx = Poly(( 1.0 - x(1,i) ),1,dca )
endif
c
c Calculate thickness.
c
if (modified) then
if (x(1,i).le.ndata(5)) then
a(1) = a(5)*sqrt( x(1,i) )
t = ndata(3)*Poly( x(1,i),3,a )
else
t = ndata(3)*Poly( (1.0-x(1,i)),3,d )
endif
else
ct(1) = 0.2969*sqrt( x(1,i) )
t = 5.0*ndata(3)*Poly( x(1,i),4,ct )
endif
c
c Finally, calculate node positions upon the foil surface.
c
dy = sqrt(( t**2 )/( 1.0+( dydx**2 )))
dx = dy * dydx
c
x(1,i) = x(1,i) + dx
x(1,j) = x(1,i) - 2.0*dx
x(2,i) = y - dy
x(2,j) = y + dy
enddo
c
c Rescale dimensions if nessisary.
c
call FoilScale( x,npt,scle )
c
return
END
c
c-----------------------------------------------------------------------------
c
SUBROUTINE Naca4b( naca,inaca,ndata,modified )
c
IMPLICIT none
INTEGER inaca
REAL ndata(5)
LOGICAL modified
CHARACTER naca*(*)
c
c This routine converts a NACA four didget number into the parameters
c describing a foil.
c
INTEGER ieps,ipmx,itau,iler,im
INTEGER Ist
EXTERNAL Ist
c
c Convert first four digits into integers.
c
inaca = Ist( 2,naca(3:3),0 )
ieps = Ist( 1,naca(1:1),0 )
ipmx = Ist( 1,naca(2:2),0 )
itau = Ist( 2,naca(3:4),0 )
ndata(1) = 0.01 * real(ieps)
ndata(2) = 0.1 * real(ipmx)
ndata(3) = 0.01 * real(itau)
c
c Check if a modified section is used.
c
if (modified) then
iler = Ist( 1,naca(6:6),6 )
im = Ist( 1,naca(7:7),3 )
ndata(4) = real(iler)
ndata(5) = 0.1 * real(im)
endif
c
return
END
c
c-----------------------------------------------------------------------------
c
SUBROUTINE Naca4c( coeff,dcoeff,camber,pmax )
c
IMPLICIT none
REAL coeff(3),dcoeff(2),camber,pmax
c
c This routine calculates the coeff's for the NACA camber equation.
c
REAL tiny
PARAMETER( tiny=1.0e-20 )
REAL inpmax
c
c
if (pmax.lt.tiny) then
inpmax = 0.0
else
inpmax = 1.0/pmax
endif
c
c
c
coeff(1) = 0.0
if (camber.lt.tiny) then
coeff(2) = 0.0
coeff(3) = 0.0
else
coeff(2) = 2.0*camber*inpmax
coeff(3) = (-camber)*(inpmax**2)
endif
dcoeff(1) = coeff(2)
dcoeff(2) = 2.0*coeff(3)
c
return
END
c
c-----------------------------------------------------------------------------
c
SUBROUTINE Naca5( x,npl,npmx,naca,inaca,scle,modified )
c
IMPLICIT none
INTEGER npl,npmx,inaca
REAL x(3,npmx),scle
CHARACTER naca*(*)
LOGICAL modified
c
c This routine calculates the ordinates of a NACA five digit foil.
c
INTEGER npt,npf
INTEGER i,j
REAL ndata(7)
REAL a(5),d(4),cl,k,m,xi,ct(5)
REAL dx,dy,dydx,t,y
REAL Poly
EXTERNAL Poly
c
DATA ct / 0.0 ,-0.126 ,-0.3537 , 0.2843 ,-0.1015 /
c
c
npt = npl+1
npf = npl/2
c
c Set the x values according to a cosine distribution.
c
call cosdn( x,npl,npmx )
c
c Calculate the parameters describing the foil, from the given NACA
c number. Then calculate the polynomial coeffs for the camber.
c
call Naca5b( naca,inaca,ndata,modified )
if (modified) then
call Nacam( a,d,ndata(6) )
endif
cl = ndata(1)
k = ndata(5)
m = ndata(4)
c
c Calculate 'y' values for each value of 'x'.
c
x(2,1) = 0.0
x(2,npt) = 0.0
x(2,npf+1) = 0.0
do i = 2,npf
j = npt+1-i
c
c Calculate the camber line.
c
xi = x(1,i)
if (xi.le.m) then
y =k*cl*( xi*xi*xi - 3.0*m*xi*xi + m*m*(3.0-m)*xi )/1.8
dydx =k*cl*( 3.0*xi*xi - 6.0*m*xi + m*m*(3.0-m) )/1.8
else
y = k*cl*m*m*m*( 1.0-xi )/1.8
dydx =-k*cl*m*m*m/1.8
endif
c
c Calculate thickness.
c
if (modified) then
if (x(1,i).le.ndata(7)) then
a(1) = a(5)*sqrt( x(1,i) )
t = ndata(3)*Poly( x(1,i),3,a )
else
t = ndata(3)*Poly( (1.0-x(1,i)),3,d )
endif
else
ct(1) = 0.2969 * sqrt( x(1,i) )
t = 5.0*ndata(3)*Poly( x(1,i),4,ct )
endif
c
c Finally, calculate node positions upon the foil surface.
c
dy = sqrt(( t**2 )/( 1.0+( dydx**2 )))
dx = dy * dydx
c
x(1,i) = x(1,i) + dx
x(1,j) = x(1,i) - 2.0*dx
x(2,i) = y - dy
x(2,j) = y + dy
enddo
c
c Rescale dimensions if nessisary.
c
call FoilScale( x,npt,scle )
c
return
END
c
c-----------------------------------------------------------------------------
c
SUBROUTINE Naca5b( naca,inaca,ndata,modified )
c
IMPLICIT none
INTEGER inaca
REAL ndata(7)
CHARACTER naca*(*)
LOGICAL modified
c
c This routine converts a NACA five didgit number into the parameters
c describing a foil.
c
INTEGER icld,ipmt,itau,iler,im
REAL c1(4),c2(6)
INTEGER Ist
REAL Poly
EXTERNAL Poly,Ist
c
DATA c1 / 0.0000, 1.0988, 1.3984, 1.8519 /
DATA c2 / 0.0000,-.0069567, .47172, 16.062,-17.409, 101.24 /
c
c Convert first four digits into integers.
c
inaca= Ist( 2,naca(4:5),0 )
icld = Ist( 1,naca(1:1),0 )
ipmt = Ist( 2,naca(2:3),0 )
itau = Ist( 2,naca(4:5),0 )
ndata(1) = 0.15*real(icld)
ndata(2) = 0.005*max( real(ipmt),1.0 )
ndata(3) = 0.01*real(itau)
ndata(4) = Poly( ndata(2),3,c1 )
ndata(5) = 1.0/( Poly( ndata(2),5,c2 ) )
c
c Check if a modified section is used.
c
if (modified) then
iler = Ist( 1,naca(7:7),6 )
im = Ist( 1,naca(8:8),3 )
ndata(6) = real(iler)
ndata(7) = 0.1*real(im)
endif
c
return
END
c
c-----------------------------------------------------------------------------
c
SUBROUTINE Nacam( a,d,ndata )
c
IMPLICIT none
REAL a(0:4),d(0:3),ndata(2)
c
c This routine calculates the coefficients for the NACA 4/5 digit
c modified thickness distributions.
c
REAL mat(3,3),vector(3)
REAL coeff(4),m,n
REAL Poly
EXTERNAL Poly,Crm3
c
DATA coeff / 1.0090,-0.24048,-2.1786, 15.833 /
c
m = ndata(2)
n = 1.0-m
c
c Calculate coefficients for the aft thickness distribution.
c
d(0) = 0.0
cc d(0) = 0.01
d(1) = Poly( m,3,coeff )
d(2) = ( 3.0*( 0.5 - d(0) ) - 2.0*d(1)*n )/( n*n )
d(3) = ( 2.0*( 0.5 - d(0) ) - 1.0*d(1)*n )/(-n*n*n )
c
c Calculate coefficients for the fore thickness.
c
a(4) = 0.24742*ndata(1)
vector(1) = 0.5 - a(4)*sqrt(m)
vector(2) =-0.5*a(4)/sqrt(m)
vector(3) = 2.*d(2) + 6.*( 1.0-m )*d(3) + 0.25*a(4)/( m**1.5 )
mat(1,1) = m
mat(1,2) = m*m
mat(1,3) = m*m*m
mat(2,1) = 1.0
mat(2,2) = 2.0*m
mat(2,3) = 3.0*m*m
mat(3,1) = 0.0
mat(3,2) = 2.0
mat(3,3) = 6.0*m
call Crm3( mat,vector,a(1) )
c
return
END